A pseudo-random number generator (PRNG) is a function g -> (a, g)
where the sequence of a
values from its repeated application to the g
values meets certain criteria. The System.Random
module of the random
package for Haskell exports a class RandomGen g
which promises functions including genWord64 :: g -> (Word64, g)
. It also exports type StdGen
and its instance of the class.
State processor
A PRNG is a state processor. In that regard, the Control.Monad.State.Lazy
module of the mtl
package exports type StateT
:
1 |
newtype StateT s (m :: * -> *) a = StateT (s -> m (a, s)) |
and type synonym State s a = StateT s Identity a
.
The modules also exports class MonadState s m
with declaration:
1 |
Monad m => MonadState s m | m -> s |
The instances of MonadState
include:
1 |
Monad m => MonadState s (StateT s m) |
Mersenne twister
The System.Random.Mersenne.Pure64
module of the mersenne-random-pure64
package exports type PureMT and its orphan instance of class RandonGen
. It also exports functions such as randomWord64 :: PureMT -> (Word64, PureMT)
.
Mutable
Some PRNG algorithms involve mutable data structures. The System.Random.Stateful
module of the random
package exports a class Monad m => StatefulGen g m
, a type StateGenM g
and an instance:
1 |
(RandomGen g, MonadState g m) => StatefulGen (StateGenM g) m |
There is an instance MonadState g (State g)
.
The following is also exported:
1 2 3 |
runStateGen :: RandomGen g => g -> (StateGenM g -> State g a) -> (a, g) runStateGen_ :: RandomGen g => g -> (StateGenM g -> State g a) -> a |
If type g
is an instance of RandomGen
and type a
is an instance of UniformRange
(see below), uniformRM
can have type StateGenM g -> State g a
, and runStateGen g
or runStateGen_ g
can be applied to it. For example (in GHCi):
1 2 3 4 5 6 7 8 |
> import Control.Monad (replicateM) > import System.Random > import System.Random.Stateful > g = mkStdGen 42 > :type g g :: StdGen > runStateGen_ g (replicateM 10 . uniformRM (0.0, 1.0)) :: [Double] [0.930852402521634,0.435276545804375,0.8854692674681801,0.8521990758897999,0.7501453784152332,0.39966266338999124,0.472367087891,0.6503106906862786,0.5617534340582975,0.11891958501343713] |
Uniform and UniformRange
Module System.Random.Stateful
also exports classes UniformRange
and Uniform
. UniformRange
promises method uniformRM :: StatefulGen g m => (a, a) -> g -> m a
, and the module exports instances of the class for commonly used types.
Uniform
promises method uniformM :: StatefulGen g m => g -> m a
, and the module exports instances of the class for commonly used types that are instances of the class Bounded
. For example, there is an instance for Int
(which is bounded) but not for Integer
(which is unbounded).
The functions provided by the instances yield uniform distributions, either from the given range ((a, a)
) or from all the values of the type a
(which is why a
has to be bounded).
Module System.Random
exports uniformR :: (RandomGen g, UniformRange a) => (a, a) -> g -> (a, g)
and uniform :: (RandomGen g, Uniform a) => g -> (a, g)
.
Marsaglia’s MWC256
The System.Random.MWC
module of the mwc-random
package exports type Gen s
and instance:
1 |
(s ~ PrimState m, PrimMonad m) => StatefulGen (Gen s) m |
It also exports create :: PrimMonad m => m (Gen (PrimState m))
, which is a generator based on a fixed seed. (IO
is an instance of PrimMonad
and PrimState m
is a type synonym associated with the class.)
For example:
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 |
module Main where import Control.Monad (replicateM) import Control.Monad.ST (RealWorld) import System.Random.MWC (GenIO, UniformRange(uniformRM), create) import Text.Printf (printf) main :: IO () main = do g <- create steps <- replicateM 10 $ step g mapM_ printLocation $ scanl add (0.0, 0.0) steps where add (x1, y1) (x2, y2) = (x1 + x2, y1 + y2) step :: GenIO -> IO (Double, Double) step g = do dx <- uniformRM (-1.0, 1.0) g dy <- uniformRM (-1.0, 1.0) g pure (dx, dy) printLocation :: (Double, Double) -> IO () printLocation (x, y) = printf "%f, %f\n" x y |